-- 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.Messaging where

import Galley.API.Update
import Galley.App
import Wire.API.Federation.API
import Wire.API.Routes.API
import Wire.API.Routes.Public.Galley.Messaging

messagingAPI :: API MessagingAPI GalleyEffects
messagingAPI :: API MessagingAPI GalleyEffects
messagingAPI =
  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 @"post-otr-message-unqualified" (((HasAnnotation 'Remote "galley" "on-message-sent",
  (HasAnnotation 'Remote "brig" "get-user-clients",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> Maybe IgnoreMissing
 -> Maybe ReportMissing
 -> NewOtrMessage
 -> 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]
      (PostOtrResponse ClientMismatch))
-> Dict (HasAnnotation 'Remote "galley" "on-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-user-clients")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Maybe IgnoreMissing
-> Maybe ReportMissing
-> NewOtrMessage
-> 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]
     (PostOtrResponse ClientMismatch)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> Maybe IgnoreMissing
 -> Maybe ReportMissing
 -> NewOtrMessage
 -> 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]
      (PostOtrResponse ClientMismatch))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Maybe IgnoreMissing
-> Maybe ReportMissing
-> NewOtrMessage
-> 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]
     (PostOtrResponse ClientMismatch)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Maybe IgnoreMissing
-> Maybe ReportMissing
-> NewOtrMessage
-> 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]
     (PostOtrResponse ClientMismatch)
forall (r :: EffectRow).
(Member BrigAccess r, Member ClientStore r,
 Member ConversationStore r, Member FederatorAccess r,
 Member BackendNotificationQueueAccess r, Member ExternalAccess r,
 Member NotificationSubsystem r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Maybe IgnoreMissing
-> Maybe ReportMissing
-> NewOtrMessage
-> Sem r (PostOtrResponse ClientMismatch)
postOtrMessageUnqualified))
    API
  (Named
     "post-otr-message-unqualified"
     (Summary
        "Post an encrypted message to a conversation (accepts JSON or Protobuf)"
      :> (Description PostOtrDescriptionUnqualified
          :> (MakesFederatedCall 'Galley "on-message-sent"
              :> (MakesFederatedCall 'Brig "get-user-clients"
                  :> (ZLocalUser
                      :> (ZConn
                          :> ("conversations"
                              :> (Capture "cnv" ConvId
                                  :> ("otr"
                                      :> ("messages"
                                          :> (QueryParam "ignore_missing" IgnoreMissing
                                              :> (QueryParam "report_missing" ReportMissing
                                                  :> (ReqBody '[JSON, Proto] NewOtrMessage
                                                      :> MultiVerb
                                                           'POST
                                                           '[JSON]
                                                           '[ErrorResponse 'ConvNotFound,
                                                             ErrorResponse 'UnknownClient,
                                                             ErrorResponse
                                                               'MissingLegalholdConsentOldClients,
                                                             ErrorResponse 'MissingLegalholdConsent,
                                                             Respond
                                                               412 "Missing clients" ClientMismatch,
                                                             Respond
                                                               201 "Message sent" ClientMismatch]
                                                           (PostOtrResponse
                                                              ClientMismatch)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "post-otr-broadcast-unqualified"
        (Summary
           "Broadcast an encrypted message to all team members and all contacts (accepts JSON or Protobuf)"
         :> (Description PostOtrDescriptionUnqualified
             :> (ZLocalUser
                 :> (ZConn
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow 'BroadcastLimitExceeded
                             :> (CanThrow 'NonBindingTeam
                                 :> ("broadcast"
                                     :> ("otr"
                                         :> ("messages"
                                             :> (QueryParam "ignore_missing" IgnoreMissing
                                                 :> (QueryParam "report_missing" ReportMissing
                                                     :> (ReqBody '[JSON, Proto] NewOtrMessage
                                                         :> MultiVerb
                                                              'POST
                                                              '[JSON]
                                                              '[ErrorResponse 'ConvNotFound,
                                                                ErrorResponse 'UnknownClient,
                                                                ErrorResponse
                                                                  'MissingLegalholdConsentOldClients,
                                                                ErrorResponse
                                                                  'MissingLegalholdConsent,
                                                                Respond
                                                                  412
                                                                  "Missing clients"
                                                                  ClientMismatch,
                                                                Respond
                                                                  201 "Message sent" ClientMismatch]
                                                              (PostOtrResponse
                                                                 ClientMismatch))))))))))))))
      :<|> (Named
              "post-proteus-message"
              (Summary
                 "Post an encrypted message to a conversation (accepts only Protobuf)"
               :> (Description PostOtrDescription
                   :> (MakesFederatedCall 'Brig "get-user-clients"
                       :> (MakesFederatedCall 'Galley "on-message-sent"
                           :> (MakesFederatedCall 'Galley "send-message"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("proteus"
                                                   :> ("messages"
                                                       :> (ReqBody
                                                             '[Proto]
                                                             (RawProto QualifiedNewOtrMessage)
                                                           :> MultiVerb
                                                                'POST
                                                                '[JSON]
                                                                '[ErrorResponse 'ConvNotFound,
                                                                  ErrorResponse 'UnknownClient,
                                                                  ErrorResponse
                                                                    'MissingLegalholdConsentOldClients,
                                                                  ErrorResponse
                                                                    'MissingLegalholdConsent,
                                                                  Respond
                                                                    412
                                                                    "Missing clients"
                                                                    MessageSendingStatus,
                                                                  Respond
                                                                    201
                                                                    "Message sent"
                                                                    MessageSendingStatus]
                                                                (Either
                                                                   (MessageNotSent
                                                                      MessageSendingStatus)
                                                                   MessageSendingStatus)))))))))))))
            :<|> Named
                   "post-proteus-broadcast"
                   (Summary
                      "Post an encrypted message to all team members and all contacts (accepts only Protobuf)"
                    :> (Description PostOtrDescription
                        :> (ZLocalUser
                            :> (ZConn
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow 'BroadcastLimitExceeded
                                        :> (CanThrow 'NonBindingTeam
                                            :> ("broadcast"
                                                :> ("proteus"
                                                    :> ("messages"
                                                        :> (ReqBody '[Proto] QualifiedNewOtrMessage
                                                            :> MultiVerb
                                                                 'POST
                                                                 '[JSON]
                                                                 '[ErrorResponse 'ConvNotFound,
                                                                   ErrorResponse 'UnknownClient,
                                                                   ErrorResponse
                                                                     'MissingLegalholdConsentOldClients,
                                                                   ErrorResponse
                                                                     'MissingLegalholdConsent,
                                                                   Respond
                                                                     412
                                                                     "Missing clients"
                                                                     MessageSendingStatus,
                                                                   Respond
                                                                     201
                                                                     "Message sent"
                                                                     MessageSendingStatus]
                                                                 (Either
                                                                    (MessageNotSent
                                                                       MessageSendingStatus)
                                                                    MessageSendingStatus))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "post-otr-message-unqualified"
        (Summary
           "Post an encrypted message to a conversation (accepts JSON or Protobuf)"
         :> (Description PostOtrDescriptionUnqualified
             :> (MakesFederatedCall 'Galley "on-message-sent"
                 :> (MakesFederatedCall 'Brig "get-user-clients"
                     :> (ZLocalUser
                         :> (ZConn
                             :> ("conversations"
                                 :> (Capture "cnv" ConvId
                                     :> ("otr"
                                         :> ("messages"
                                             :> (QueryParam "ignore_missing" IgnoreMissing
                                                 :> (QueryParam "report_missing" ReportMissing
                                                     :> (ReqBody '[JSON, Proto] NewOtrMessage
                                                         :> MultiVerb
                                                              'POST
                                                              '[JSON]
                                                              '[ErrorResponse 'ConvNotFound,
                                                                ErrorResponse 'UnknownClient,
                                                                ErrorResponse
                                                                  'MissingLegalholdConsentOldClients,
                                                                ErrorResponse
                                                                  'MissingLegalholdConsent,
                                                                Respond
                                                                  412
                                                                  "Missing clients"
                                                                  ClientMismatch,
                                                                Respond
                                                                  201 "Message sent" ClientMismatch]
                                                              (PostOtrResponse
                                                                 ClientMismatch))))))))))))))
      :<|> (Named
              "post-otr-broadcast-unqualified"
              (Summary
                 "Broadcast an encrypted message to all team members and all contacts (accepts JSON or Protobuf)"
               :> (Description PostOtrDescriptionUnqualified
                   :> (ZLocalUser
                       :> (ZConn
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow 'BroadcastLimitExceeded
                                   :> (CanThrow 'NonBindingTeam
                                       :> ("broadcast"
                                           :> ("otr"
                                               :> ("messages"
                                                   :> (QueryParam "ignore_missing" IgnoreMissing
                                                       :> (QueryParam "report_missing" ReportMissing
                                                           :> (ReqBody '[JSON, Proto] NewOtrMessage
                                                               :> MultiVerb
                                                                    'POST
                                                                    '[JSON]
                                                                    '[ErrorResponse 'ConvNotFound,
                                                                      ErrorResponse 'UnknownClient,
                                                                      ErrorResponse
                                                                        'MissingLegalholdConsentOldClients,
                                                                      ErrorResponse
                                                                        'MissingLegalholdConsent,
                                                                      Respond
                                                                        412
                                                                        "Missing clients"
                                                                        ClientMismatch,
                                                                      Respond
                                                                        201
                                                                        "Message sent"
                                                                        ClientMismatch]
                                                                    (PostOtrResponse
                                                                       ClientMismatch))))))))))))))
            :<|> (Named
                    "post-proteus-message"
                    (Summary
                       "Post an encrypted message to a conversation (accepts only Protobuf)"
                     :> (Description PostOtrDescription
                         :> (MakesFederatedCall 'Brig "get-user-clients"
                             :> (MakesFederatedCall 'Galley "on-message-sent"
                                 :> (MakesFederatedCall 'Galley "send-message"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("proteus"
                                                         :> ("messages"
                                                             :> (ReqBody
                                                                   '[Proto]
                                                                   (RawProto QualifiedNewOtrMessage)
                                                                 :> MultiVerb
                                                                      'POST
                                                                      '[JSON]
                                                                      '[ErrorResponse 'ConvNotFound,
                                                                        ErrorResponse
                                                                          'UnknownClient,
                                                                        ErrorResponse
                                                                          'MissingLegalholdConsentOldClients,
                                                                        ErrorResponse
                                                                          'MissingLegalholdConsent,
                                                                        Respond
                                                                          412
                                                                          "Missing clients"
                                                                          MessageSendingStatus,
                                                                        Respond
                                                                          201
                                                                          "Message sent"
                                                                          MessageSendingStatus]
                                                                      (Either
                                                                         (MessageNotSent
                                                                            MessageSendingStatus)
                                                                         MessageSendingStatus)))))))))))))
                  :<|> Named
                         "post-proteus-broadcast"
                         (Summary
                            "Post an encrypted message to all team members and all contacts (accepts only Protobuf)"
                          :> (Description PostOtrDescription
                              :> (ZLocalUser
                                  :> (ZConn
                                      :> (CanThrow 'TeamNotFound
                                          :> (CanThrow 'BroadcastLimitExceeded
                                              :> (CanThrow 'NonBindingTeam
                                                  :> ("broadcast"
                                                      :> ("proteus"
                                                          :> ("messages"
                                                              :> (ReqBody
                                                                    '[Proto] QualifiedNewOtrMessage
                                                                  :> MultiVerb
                                                                       'POST
                                                                       '[JSON]
                                                                       '[ErrorResponse
                                                                           'ConvNotFound,
                                                                         ErrorResponse
                                                                           'UnknownClient,
                                                                         ErrorResponse
                                                                           'MissingLegalholdConsentOldClients,
                                                                         ErrorResponse
                                                                           'MissingLegalholdConsent,
                                                                         Respond
                                                                           412
                                                                           "Missing clients"
                                                                           MessageSendingStatus,
                                                                         Respond
                                                                           201
                                                                           "Message sent"
                                                                           MessageSendingStatus]
                                                                       (Either
                                                                          (MessageNotSent
                                                                             MessageSendingStatus)
                                                                          MessageSendingStatus)))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"post-otr-broadcast-unqualified" ServerT
  (Summary
     "Broadcast an encrypted message to all team members and all contacts (accepts JSON or Protobuf)"
   :> (Description PostOtrDescriptionUnqualified
       :> (ZLocalUser
           :> (ZConn
               :> (CanThrow 'TeamNotFound
                   :> (CanThrow 'BroadcastLimitExceeded
                       :> (CanThrow 'NonBindingTeam
                           :> ("broadcast"
                               :> ("otr"
                                   :> ("messages"
                                       :> (QueryParam "ignore_missing" IgnoreMissing
                                           :> (QueryParam "report_missing" ReportMissing
                                               :> (ReqBody '[JSON, Proto] NewOtrMessage
                                                   :> MultiVerb
                                                        'POST
                                                        '[JSON]
                                                        '[ErrorResponse 'ConvNotFound,
                                                          ErrorResponse 'UnknownClient,
                                                          ErrorResponse
                                                            'MissingLegalholdConsentOldClients,
                                                          ErrorResponse 'MissingLegalholdConsent,
                                                          Respond
                                                            412 "Missing clients" ClientMismatch,
                                                          Respond 201 "Message sent" ClientMismatch]
                                                        (PostOtrResponse
                                                           ClientMismatch))))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "Broadcast an encrypted message to all team members and all contacts (accepts JSON or Protobuf)"
            :> (Description PostOtrDescriptionUnqualified
                :> (ZLocalUser
                    :> (ZConn
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow 'BroadcastLimitExceeded
                                :> (CanThrow 'NonBindingTeam
                                    :> ("broadcast"
                                        :> ("otr"
                                            :> ("messages"
                                                :> (QueryParam "ignore_missing" IgnoreMissing
                                                    :> (QueryParam "report_missing" ReportMissing
                                                        :> (ReqBody '[JSON, Proto] NewOtrMessage
                                                            :> MultiVerb
                                                                 'POST
                                                                 '[JSON]
                                                                 '[ErrorResponse 'ConvNotFound,
                                                                   ErrorResponse 'UnknownClient,
                                                                   ErrorResponse
                                                                     'MissingLegalholdConsentOldClients,
                                                                   ErrorResponse
                                                                     'MissingLegalholdConsent,
                                                                   Respond
                                                                     412
                                                                     "Missing clients"
                                                                     ClientMismatch,
                                                                   Respond
                                                                     201
                                                                     "Message sent"
                                                                     ClientMismatch]
                                                                 (PostOtrResponse
                                                                    ClientMismatch)))))))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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
-> Maybe IgnoreMissing
-> Maybe ReportMissing
-> NewOtrMessage
-> Sem
     '[Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'BroadcastLimitExceeded ()),
       Error (Tagged 'NonBindingTeam ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (PostOtrResponse ClientMismatch)
forall (r :: EffectRow).
(Member BrigAccess r, Member ClientStore r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged 'NonBindingTeam ())) r,
 Member (Error (Tagged 'BroadcastLimitExceeded ())) r,
 Member NotificationSubsystem r, Member ExternalAccess r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member TeamStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Maybe IgnoreMissing
-> Maybe ReportMissing
-> NewOtrMessage
-> Sem r (PostOtrResponse ClientMismatch)
postOtrBroadcastUnqualified
    API
  (Named
     "post-otr-broadcast-unqualified"
     (Summary
        "Broadcast an encrypted message to all team members and all contacts (accepts JSON or Protobuf)"
      :> (Description PostOtrDescriptionUnqualified
          :> (ZLocalUser
              :> (ZConn
                  :> (CanThrow 'TeamNotFound
                      :> (CanThrow 'BroadcastLimitExceeded
                          :> (CanThrow 'NonBindingTeam
                              :> ("broadcast"
                                  :> ("otr"
                                      :> ("messages"
                                          :> (QueryParam "ignore_missing" IgnoreMissing
                                              :> (QueryParam "report_missing" ReportMissing
                                                  :> (ReqBody '[JSON, Proto] NewOtrMessage
                                                      :> MultiVerb
                                                           'POST
                                                           '[JSON]
                                                           '[ErrorResponse 'ConvNotFound,
                                                             ErrorResponse 'UnknownClient,
                                                             ErrorResponse
                                                               'MissingLegalholdConsentOldClients,
                                                             ErrorResponse 'MissingLegalholdConsent,
                                                             Respond
                                                               412 "Missing clients" ClientMismatch,
                                                             Respond
                                                               201 "Message sent" ClientMismatch]
                                                           (PostOtrResponse
                                                              ClientMismatch)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "post-proteus-message"
        (Summary
           "Post an encrypted message to a conversation (accepts only Protobuf)"
         :> (Description PostOtrDescription
             :> (MakesFederatedCall 'Brig "get-user-clients"
                 :> (MakesFederatedCall 'Galley "on-message-sent"
                     :> (MakesFederatedCall 'Galley "send-message"
                         :> (ZLocalUser
                             :> (ZConn
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("proteus"
                                             :> ("messages"
                                                 :> (ReqBody
                                                       '[Proto] (RawProto QualifiedNewOtrMessage)
                                                     :> MultiVerb
                                                          'POST
                                                          '[JSON]
                                                          '[ErrorResponse 'ConvNotFound,
                                                            ErrorResponse 'UnknownClient,
                                                            ErrorResponse
                                                              'MissingLegalholdConsentOldClients,
                                                            ErrorResponse 'MissingLegalholdConsent,
                                                            Respond
                                                              412
                                                              "Missing clients"
                                                              MessageSendingStatus,
                                                            Respond
                                                              201
                                                              "Message sent"
                                                              MessageSendingStatus]
                                                          (Either
                                                             (MessageNotSent MessageSendingStatus)
                                                             MessageSendingStatus)))))))))))))
      :<|> Named
             "post-proteus-broadcast"
             (Summary
                "Post an encrypted message to all team members and all contacts (accepts only Protobuf)"
              :> (Description PostOtrDescription
                  :> (ZLocalUser
                      :> (ZConn
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow 'BroadcastLimitExceeded
                                  :> (CanThrow 'NonBindingTeam
                                      :> ("broadcast"
                                          :> ("proteus"
                                              :> ("messages"
                                                  :> (ReqBody '[Proto] QualifiedNewOtrMessage
                                                      :> MultiVerb
                                                           'POST
                                                           '[JSON]
                                                           '[ErrorResponse 'ConvNotFound,
                                                             ErrorResponse 'UnknownClient,
                                                             ErrorResponse
                                                               'MissingLegalholdConsentOldClients,
                                                             ErrorResponse 'MissingLegalholdConsent,
                                                             Respond
                                                               412
                                                               "Missing clients"
                                                               MessageSendingStatus,
                                                             Respond
                                                               201
                                                               "Message sent"
                                                               MessageSendingStatus]
                                                           (Either
                                                              (MessageNotSent MessageSendingStatus)
                                                              MessageSendingStatus)))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "post-otr-broadcast-unqualified"
        (Summary
           "Broadcast an encrypted message to all team members and all contacts (accepts JSON or Protobuf)"
         :> (Description PostOtrDescriptionUnqualified
             :> (ZLocalUser
                 :> (ZConn
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow 'BroadcastLimitExceeded
                             :> (CanThrow 'NonBindingTeam
                                 :> ("broadcast"
                                     :> ("otr"
                                         :> ("messages"
                                             :> (QueryParam "ignore_missing" IgnoreMissing
                                                 :> (QueryParam "report_missing" ReportMissing
                                                     :> (ReqBody '[JSON, Proto] NewOtrMessage
                                                         :> MultiVerb
                                                              'POST
                                                              '[JSON]
                                                              '[ErrorResponse 'ConvNotFound,
                                                                ErrorResponse 'UnknownClient,
                                                                ErrorResponse
                                                                  'MissingLegalholdConsentOldClients,
                                                                ErrorResponse
                                                                  'MissingLegalholdConsent,
                                                                Respond
                                                                  412
                                                                  "Missing clients"
                                                                  ClientMismatch,
                                                                Respond
                                                                  201 "Message sent" ClientMismatch]
                                                              (PostOtrResponse
                                                                 ClientMismatch))))))))))))))
      :<|> (Named
              "post-proteus-message"
              (Summary
                 "Post an encrypted message to a conversation (accepts only Protobuf)"
               :> (Description PostOtrDescription
                   :> (MakesFederatedCall 'Brig "get-user-clients"
                       :> (MakesFederatedCall 'Galley "on-message-sent"
                           :> (MakesFederatedCall 'Galley "send-message"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("proteus"
                                                   :> ("messages"
                                                       :> (ReqBody
                                                             '[Proto]
                                                             (RawProto QualifiedNewOtrMessage)
                                                           :> MultiVerb
                                                                'POST
                                                                '[JSON]
                                                                '[ErrorResponse 'ConvNotFound,
                                                                  ErrorResponse 'UnknownClient,
                                                                  ErrorResponse
                                                                    'MissingLegalholdConsentOldClients,
                                                                  ErrorResponse
                                                                    'MissingLegalholdConsent,
                                                                  Respond
                                                                    412
                                                                    "Missing clients"
                                                                    MessageSendingStatus,
                                                                  Respond
                                                                    201
                                                                    "Message sent"
                                                                    MessageSendingStatus]
                                                                (Either
                                                                   (MessageNotSent
                                                                      MessageSendingStatus)
                                                                   MessageSendingStatus)))))))))))))
            :<|> Named
                   "post-proteus-broadcast"
                   (Summary
                      "Post an encrypted message to all team members and all contacts (accepts only Protobuf)"
                    :> (Description PostOtrDescription
                        :> (ZLocalUser
                            :> (ZConn
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow 'BroadcastLimitExceeded
                                        :> (CanThrow 'NonBindingTeam
                                            :> ("broadcast"
                                                :> ("proteus"
                                                    :> ("messages"
                                                        :> (ReqBody '[Proto] QualifiedNewOtrMessage
                                                            :> MultiVerb
                                                                 'POST
                                                                 '[JSON]
                                                                 '[ErrorResponse 'ConvNotFound,
                                                                   ErrorResponse 'UnknownClient,
                                                                   ErrorResponse
                                                                     'MissingLegalholdConsentOldClients,
                                                                   ErrorResponse
                                                                     'MissingLegalholdConsent,
                                                                   Respond
                                                                     412
                                                                     "Missing clients"
                                                                     MessageSendingStatus,
                                                                   Respond
                                                                     201
                                                                     "Message sent"
                                                                     MessageSendingStatus]
                                                                 (Either
                                                                    (MessageNotSent
                                                                       MessageSendingStatus)
                                                                    MessageSendingStatus))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"post-proteus-message" (((HasAnnotation 'Remote "brig" "get-user-clients",
  (HasAnnotation 'Remote "galley" "on-message-sent",
   (HasAnnotation 'Remote "galley" "send-message",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> RawProto QualifiedNewOtrMessage
 -> 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]
      (Either
         (MessageNotSent MessageSendingStatus) MessageSendingStatus))
-> Dict (HasAnnotation 'Remote "brig" "get-user-clients")
-> Dict (HasAnnotation 'Remote "galley" "on-message-sent")
-> Dict (HasAnnotation 'Remote "galley" "send-message")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> RawProto QualifiedNewOtrMessage
-> 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]
     (Either (MessageNotSent MessageSendingStatus) MessageSendingStatus)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> RawProto QualifiedNewOtrMessage
 -> 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]
      (Either
         (MessageNotSent MessageSendingStatus) MessageSendingStatus))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> RawProto QualifiedNewOtrMessage
-> 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]
     (Either (MessageNotSent MessageSendingStatus) MessageSendingStatus)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> RawProto QualifiedNewOtrMessage
-> 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]
     (Either (MessageNotSent MessageSendingStatus) MessageSendingStatus)
forall (r :: EffectRow).
(Member BrigAccess r, Member ClientStore r,
 Member ConversationStore r, Member FederatorAccess r,
 Member BackendNotificationQueueAccess r,
 Member NotificationSubsystem r, Member ExternalAccess r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member TeamStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> RawProto QualifiedNewOtrMessage
-> Sem
     r
     (Either (MessageNotSent MessageSendingStatus) MessageSendingStatus)
postProteusMessage))
    API
  (Named
     "post-proteus-message"
     (Summary
        "Post an encrypted message to a conversation (accepts only Protobuf)"
      :> (Description PostOtrDescription
          :> (MakesFederatedCall 'Brig "get-user-clients"
              :> (MakesFederatedCall 'Galley "on-message-sent"
                  :> (MakesFederatedCall 'Galley "send-message"
                      :> (ZLocalUser
                          :> (ZConn
                              :> ("conversations"
                                  :> (QualifiedCapture "cnv" ConvId
                                      :> ("proteus"
                                          :> ("messages"
                                              :> (ReqBody '[Proto] (RawProto QualifiedNewOtrMessage)
                                                  :> MultiVerb
                                                       'POST
                                                       '[JSON]
                                                       '[ErrorResponse 'ConvNotFound,
                                                         ErrorResponse 'UnknownClient,
                                                         ErrorResponse
                                                           'MissingLegalholdConsentOldClients,
                                                         ErrorResponse 'MissingLegalholdConsent,
                                                         Respond
                                                           412
                                                           "Missing clients"
                                                           MessageSendingStatus,
                                                         Respond
                                                           201 "Message sent" MessageSendingStatus]
                                                       (Either
                                                          (MessageNotSent MessageSendingStatus)
                                                          MessageSendingStatus))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (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
        "post-proteus-broadcast"
        (Summary
           "Post an encrypted message to all team members and all contacts (accepts only Protobuf)"
         :> (Description PostOtrDescription
             :> (ZLocalUser
                 :> (ZConn
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow 'BroadcastLimitExceeded
                             :> (CanThrow 'NonBindingTeam
                                 :> ("broadcast"
                                     :> ("proteus"
                                         :> ("messages"
                                             :> (ReqBody '[Proto] QualifiedNewOtrMessage
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[ErrorResponse 'ConvNotFound,
                                                        ErrorResponse 'UnknownClient,
                                                        ErrorResponse
                                                          'MissingLegalholdConsentOldClients,
                                                        ErrorResponse 'MissingLegalholdConsent,
                                                        Respond
                                                          412
                                                          "Missing clients"
                                                          MessageSendingStatus,
                                                        Respond
                                                          201 "Message sent" MessageSendingStatus]
                                                      (Either
                                                         (MessageNotSent MessageSendingStatus)
                                                         MessageSendingStatus)))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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
        "post-proteus-message"
        (Summary
           "Post an encrypted message to a conversation (accepts only Protobuf)"
         :> (Description PostOtrDescription
             :> (MakesFederatedCall 'Brig "get-user-clients"
                 :> (MakesFederatedCall 'Galley "on-message-sent"
                     :> (MakesFederatedCall 'Galley "send-message"
                         :> (ZLocalUser
                             :> (ZConn
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("proteus"
                                             :> ("messages"
                                                 :> (ReqBody
                                                       '[Proto] (RawProto QualifiedNewOtrMessage)
                                                     :> MultiVerb
                                                          'POST
                                                          '[JSON]
                                                          '[ErrorResponse 'ConvNotFound,
                                                            ErrorResponse 'UnknownClient,
                                                            ErrorResponse
                                                              'MissingLegalholdConsentOldClients,
                                                            ErrorResponse 'MissingLegalholdConsent,
                                                            Respond
                                                              412
                                                              "Missing clients"
                                                              MessageSendingStatus,
                                                            Respond
                                                              201
                                                              "Message sent"
                                                              MessageSendingStatus]
                                                          (Either
                                                             (MessageNotSent MessageSendingStatus)
                                                             MessageSendingStatus)))))))))))))
      :<|> Named
             "post-proteus-broadcast"
             (Summary
                "Post an encrypted message to all team members and all contacts (accepts only Protobuf)"
              :> (Description PostOtrDescription
                  :> (ZLocalUser
                      :> (ZConn
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow 'BroadcastLimitExceeded
                                  :> (CanThrow 'NonBindingTeam
                                      :> ("broadcast"
                                          :> ("proteus"
                                              :> ("messages"
                                                  :> (ReqBody '[Proto] QualifiedNewOtrMessage
                                                      :> MultiVerb
                                                           'POST
                                                           '[JSON]
                                                           '[ErrorResponse 'ConvNotFound,
                                                             ErrorResponse 'UnknownClient,
                                                             ErrorResponse
                                                               'MissingLegalholdConsentOldClients,
                                                             ErrorResponse 'MissingLegalholdConsent,
                                                             Respond
                                                               412
                                                               "Missing clients"
                                                               MessageSendingStatus,
                                                             Respond
                                                               201
                                                               "Message sent"
                                                               MessageSendingStatus]
                                                           (Either
                                                              (MessageNotSent MessageSendingStatus)
                                                              MessageSendingStatus)))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 @"post-proteus-broadcast" ServerT
  (Summary
     "Post an encrypted message to all team members and all contacts (accepts only Protobuf)"
   :> (Description PostOtrDescription
       :> (ZLocalUser
           :> (ZConn
               :> (CanThrow 'TeamNotFound
                   :> (CanThrow 'BroadcastLimitExceeded
                       :> (CanThrow 'NonBindingTeam
                           :> ("broadcast"
                               :> ("proteus"
                                   :> ("messages"
                                       :> (ReqBody '[Proto] QualifiedNewOtrMessage
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[ErrorResponse 'ConvNotFound,
                                                  ErrorResponse 'UnknownClient,
                                                  ErrorResponse 'MissingLegalholdConsentOldClients,
                                                  ErrorResponse 'MissingLegalholdConsent,
                                                  Respond
                                                    412 "Missing clients" MessageSendingStatus,
                                                  Respond 201 "Message sent" MessageSendingStatus]
                                                (Either
                                                   (MessageNotSent MessageSendingStatus)
                                                   MessageSendingStatus))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "Post an encrypted message to all team members and all contacts (accepts only Protobuf)"
            :> (Description PostOtrDescription
                :> (ZLocalUser
                    :> (ZConn
                        :> (CanThrow 'TeamNotFound
                            :> (CanThrow 'BroadcastLimitExceeded
                                :> (CanThrow 'NonBindingTeam
                                    :> ("broadcast"
                                        :> ("proteus"
                                            :> ("messages"
                                                :> (ReqBody '[Proto] QualifiedNewOtrMessage
                                                    :> MultiVerb
                                                         'POST
                                                         '[JSON]
                                                         '[ErrorResponse 'ConvNotFound,
                                                           ErrorResponse 'UnknownClient,
                                                           ErrorResponse
                                                             'MissingLegalholdConsentOldClients,
                                                           ErrorResponse 'MissingLegalholdConsent,
                                                           Respond
                                                             412
                                                             "Missing clients"
                                                             MessageSendingStatus,
                                                           Respond
                                                             201
                                                             "Message sent"
                                                             MessageSendingStatus]
                                                         (Either
                                                            (MessageNotSent MessageSendingStatus)
                                                            MessageSendingStatus)))))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (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
-> QualifiedNewOtrMessage
-> Sem
     '[Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'BroadcastLimitExceeded ()),
       Error (Tagged 'NonBindingTeam ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (Either (MessageNotSent MessageSendingStatus) MessageSendingStatus)
forall (r :: EffectRow).
(Member BrigAccess r, Member ClientStore r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged 'NonBindingTeam ())) r,
 Member (Error (Tagged 'BroadcastLimitExceeded ())) r,
 Member NotificationSubsystem r, Member ExternalAccess r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member TeamStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> QualifiedNewOtrMessage
-> Sem
     r
     (Either (MessageNotSent MessageSendingStatus) MessageSendingStatus)
postProteusBroadcast